home *** CD-ROM | disk | FTP | other *** search
/ Libris Britannia 4 / science library(b).zip / science library(b) / SCIENTIF / 0807.ZIP / GALILEAN.BAS < prev    next >
BASIC Source File  |  1987-09-30  |  13KB  |  463 lines

  1. ' Program "GALILEAN"
  2.  
  3. ' copyright (C) 1986 by David Eagle
  4.  
  5. ' public domain for IBM-PC on November 23, 1986
  6.  
  7. ' IBM-PC  << QuickBASIC Compiler Version 3.0 >>
  8.  
  9. ' determines position of Jupiter's great satellites
  10.  
  11. ' x-position (positive west of Jupiter; units of Jupiter radii)
  12. ' y-position (positive north of Jupiter; units of Jupiter radii)
  13. ' position angle (relative to inferior junction with Jupiter; degrees)
  14. ' Jupiter semi-diameter (units of arc seconds)
  15. ' Julian Date
  16.  
  17. '********************************************************************
  18.  
  19. OPTION BASE 1
  20. DEFDBL A-Z
  21.  
  22. DIM SHARED MONTH$(12),SATELLITE$(4),R(4),X(4),Y(4),U(4)
  23.  
  24. COMMON SHARED JULIAN.DATE0,HOUR%,MINUTE%,LCT$,MONTH%,DAY%,YEAR%
  25. COMMON SHARED DST%,ZONE%,JULIAN.DATE,SEMIDIAMETER,CDATE$,TDELAY
  26.  
  27. CONST PI=3.141592653589793D0
  28. CONST PIDIV2=.5D0*PI
  29. CONST PI2=2D0*PI
  30. CONST RTD=180D0/PI
  31.  
  32. DEF FNMOD(X)=X-PI2*INT(X/PI2)
  33.  
  34. DEF FNJDATE(MONTH%,DAY%,YEAR%)
  35.     'JULIAN Date function
  36.     F=367D0*YEAR%-INT(7*((YEAR%+INT((MONTH%+9)/12))/4))
  37.     F=F+INT(275*MONTH%/9)+DAY%+1721028.5D0
  38.     FNJDATE=F-INT(3*(INT((YEAR%+SGN(MONTH%-9)*INT(ABS((MONTH%-9)/7)))/100)+1)/4)
  39. END DEF
  40.  
  41. DEF FNASN(X)
  42.     ' inverse sine function
  43.     IF ABS(X)>=1D0 THEN
  44.        FNASN=SGN(SINANGLE)*PIDIV2
  45.     ELSE
  46.        FNASN=ATN(X/SQR(1D0-X^2))
  47.     END IF
  48. END DEF
  49.  
  50. ' calendar months
  51.  
  52. MONTH$(1)="January"
  53. MONTH$(2)="February"
  54. MONTH$(3)="March"
  55. MONTH$(4)="April"
  56. MONTH$(5)="May"
  57. MONTH$(6)="June"
  58. MONTH$(7)="July"
  59. MONTH$(8)="August"
  60. MONTH$(9)="September"
  61. MONTH$(10)="October"
  62. MONTH$(11)="November"
  63. MONTH$(12)="December"
  64.  
  65. ' satellite names
  66.  
  67. SATELLITE$(1)="Io"
  68. SATELLITE$(2)="Europa"
  69. SATELLITE$(3)="Ganymede"
  70. SATELLITE$(4)="Callisto"
  71.  
  72. TDELAY=10
  73.  
  74. '********************************************************************
  75.  
  76. CLS
  77. PRINT
  78. PRINT "Program Galilean"
  79. PRINT "(C) Copyright 1986 by David Eagle"
  80. PRINT
  81. PRINT "Microsoft QuickBasic Compiler"
  82. PRINT "(C) Copyright Microsoft Corp. 1982-1987"
  83. PRINT
  84. CALL KEYCHECK
  85.  
  86. CLS
  87. PRINT
  88. PRINT
  89. INPUT "Program introduction ( y = yes, n = no ) ";INTRO$
  90. IF INSTR("yY",INTRO$) THEN CALL INTRODUCTION
  91.  
  92. DO
  93.    CLS
  94.    PRINT
  95.    PRINT
  96.    PRINT
  97.    PRINT "Calendar date ( month [ 1 - 12 ], day [ 1 - 31 ], year [ YYYY ] )"
  98.    PRINT "< NOTE: B.C. dates are negative, A.D. dates are positive >"
  99.    PRINT "< For example, October 21, 1986 is input as 10,21,1986 >"
  100.    INPUT MONTH%,DAY%,YEAR%
  101.    PRINT
  102.    PRINT "Local civil time ( hours [ 0 - 23 ], minutes [ 0 - 59 ] )"
  103.    PRINT "< For example, 8:30 pm is input as 20,30 >"
  104.    INPUT HOUR%,MINUTE%
  105.    PRINT
  106.    PRINT "Time zone ( 0 - 23 )"
  107.    PRINT "< For example, Mountain Standard Time (MST) is time zone 7 >"
  108.    INPUT ZONE%
  109.    PRINT
  110.    PRINT "Daylight Savings Time ( y = yes, n = no )"
  111.    INPUT DST.FLAG$
  112.    IF INSTR("yY",DST.FLAG$) THEN
  113.       DST%=1
  114.    ELSE
  115.       DST%=0
  116.    END IF
  117.  
  118.    JULIAN.DATE0=FNJDATE(MONTH%,DAY%,YEAR%)
  119.    CALL MAIN.DRIVER
  120.  
  121.    CLS
  122.    PRINT
  123.    PRINT
  124.    PRINT "Another selection ( y = yes, n = no )"
  125.    INPUT SELECTION$
  126. LOOP UNTIL INSTR("nN",SELECTION$)
  127.  
  128. END
  129.  
  130. '********************************************************************
  131.  
  132. SUB MAIN.DRIVER STATIC
  133.  
  134.     ' main driver subroutine
  135.  
  136.     FIRSTPASS$="TRUE"
  137.     RESPONSE%=0
  138.     JULIAN.DATE0=JULIAN.DATE0-1D0
  139.     LCT$=STR$(HOUR%)+" hours "+STR$(MINUTE%)+" minutes"
  140.     WHILE RESPONSE%<>4
  141.       RESPONSE%=0
  142.       WHILE RESPONSE%<=0 OR RESPONSE%>5
  143.         CLS
  144.         CALL SELECTION.MENU(RESPONSE%)
  145.       WEND
  146.       IF RESPONSE%=3 OR FIRSTPASS$="TRUE" THEN
  147.          JULIAN.DATE0=JULIAN.DATE0+1D0
  148.          CALL GREGORIAN.DATE(JULIAN.DATE0+.5D0)
  149.          CALL SAT.POSITIONS
  150.       END IF
  151.  
  152.       IF RESPONSE%=1 THEN CALL DISPLAY.DATA
  153.       IF RESPONSE%=2 THEN CALL GRAPHICS
  154.  
  155.       FIRSTPASS$="FALSE"
  156.     WEND
  157.  
  158. END SUB
  159.  
  160. '********************************************************************
  161.  
  162. SUB ELAPSED.DAYS(EDAYS) STATIC
  163.  
  164.     ' elapsed days subroutine
  165.  
  166.     GMT=HOUR%+MINUTE%/60D0-DST%+ZONE%
  167.     A=(JULIAN.DATE0-2415020D0)/36525D0
  168.     JULIAN.DATE=JULIAN.DATE0+GMT/24D0+(.41D0+1.2053D0*A+.4992D0*A^2)/1440D0
  169.     EDAYS=JULIAN.DATE-2415020D0
  170.  
  171. END SUB
  172.  
  173. '********************************************************************
  174.  
  175. SUB SAT.POSITIONS STATIC
  176.  
  177.     ' satellite positions subroutine
  178.  
  179.     CALL ELAPSED.DAYS(D2)
  180.     V=FNMOD(2.34974D0+.0000194756D0*D2)
  181.     M=FNMOD(6.256586D0+.01720197D0*D2)
  182.     N=FNMOD(3.93272126D0+.0014501127D0*D2+.00576D0*SIN(V))
  183.     J=FNMOD(3.8684699D0+.015751909D0*D2-.00576D0*SIN(V))
  184.     O=FNMOD(.0334405D0*SIN(M)+.000349D0*SIN(2D0*M))
  185.     P=FNMOD(.0969007D0*SIN(N)+.0029147D0*SIN(2D0*N))
  186.     K=FNMOD(J+O-P)
  187.     R1=1.00014D0-.01672D0*COS(M)-.0014D0*COS(2D0*M)
  188.     R2=5.20867D0-.25192D0*COS(N)-.0061D0*COS(2D0*N)
  189.     D3=SQR(R1^2+R2^2-2D0*R1*R2*COS(K))
  190.     S4=FNASN(.00047726615D0/D3)
  191.     SEMIDIAMETER=206264.806D0*S4
  192.     S2=R1*SIN(K)/D3
  193.     S3=FNASN(S2)
  194.     L1=4.154756D0+.0014502D0*D2+.00576D0*SIN(V)+P
  195.     A=.05358D0*SIN(L1+.77667D0)
  196.     D4=A-.03752D0*S2*COS(L1+.4189D0)-.02286D0*((R2-D3)/D3)*SIN(L1-1.73486D0)
  197.     A=D2-D3/173.1446D0
  198.     U(1)=FNMOD(1.475686D0+3.550102027D0*A+S3-P)
  199.     U(2)=FNMOD(.724338D0+1.767872488D0*A+S3-P)
  200.     U(3)=FNMOD(1.9194607D0+.876757718D0*A+S3-P)
  201.     U(4)=FNMOD(3.07803823D0+.375036004D0*A+S3-P)
  202.     G=FNMOD(3.269D0+.87808691D0*A)
  203.     H=FNMOD(5.4297D0+.376454063D0*A)
  204.     R(1)=5.9061D0-.0244D0*COS(2D0*(U(1)-U(2)))
  205.     R(2)=9.3972D0-.0889D0*COS(2D0*(U(2)-U(3)))
  206.     R(3)=14.9894D0-.0227D0*COS(G)
  207.     R(4)=26.3649D0-.1944D0*COS(H)
  208.     U(1)=FNMOD(U(1)+.0082296D0*SIN(2D0*(U(1)-U(2))))
  209.     U(2)=FNMOD(U(2)+.018727D0*SIN(2D0*(U(2)-U(3))))
  210.     U(3)=FNMOD(U(3)+.003037D0*SIN(G))
  211.     U(4)=FNMOD(U(4)+.014748D0*SIN(H))
  212.     FOR I%=1 TO 4
  213.         X(I%)=R(I%)*SIN(U(I%))
  214.         Y(I%)=-R(I%)*COS(U(I%))*SIN(D4)
  215.     NEXT I%
  216.  
  217. END SUB
  218.  
  219. '********************************************************************
  220.  
  221. SUB GREGORIAN.DATE(JDATE) STATIC
  222.  
  223.     ' Gregorian Date subroutine
  224.  
  225.     IF JDATE<2299161D0 THEN
  226.        A=JDATE
  227.     ELSE
  228.        A=INT((JDATE-1867216.25D0)/36524.25)
  229.        A=JDATE+A-INT(A/4)+1D0
  230.     END IF
  231.     B=A+1524D0
  232.     C=INT((B-122.1)/365.25D0)
  233.     D=INT(365.25D0*C)
  234.     E=INT((B-D)/30.6001D0)
  235.     DAY%=B-D-INT(30.6001D0*E)
  236.     IF E<13.5 THEN
  237.        MONTH%=E-1
  238.     ELSE
  239.        MONTH%=E-13
  240.     END IF
  241.  
  242.     IF MONTH%>2.5 THEN
  243.        YEAR%=C-4716
  244.     ELSE
  245.        YEAR%=C-4715
  246.     END IF
  247.  
  248.     CDATE$=MONTH$(MONTH%)+STR$(DAY%)+","+STR$(YEAR%)
  249.  
  250. END SUB
  251.  
  252. '********************************************************************
  253.  
  254. SUB SELECTION.MENU(SELECTION%) STATIC
  255.  
  256.     ' selection menu subroutine
  257.  
  258.     CLS
  259.     PRINT
  260.     PRINT
  261.     PRINT "                           *** Please Note ***"
  262.     PRINT
  263.     PRINT
  264.     PRINT "   After a data or graphics display page appears on the screen, it may"
  265.     PRINT "  be saved to a printer by pressing the <Shift> <PrtSc> key combination."
  266.     PRINT
  267.     PRINT "   Printing a graphics screen requires that the program 'GRAPHICS.COM'"
  268.     PRINT "      from the system disk be executed before running this program."
  269.     PRINT
  270.     PRINT "   The program will automatically display data or graphics screens every"
  271.     PRINT TDELAY;"seconds. The user may manually cycle the screen by pressing any key."
  272.     PRINT
  273.     PRINT
  274.     PRINT
  275.     PRINT "Would you like to change the screen display interval ( y = yes, n = no )"
  276.     INPUT A$
  277.     IF INSTR("yY",A$) THEN
  278.        PRINT
  279.        PRINT
  280.        INPUT "New time interval ( seconds )";TDELAY
  281.     END IF
  282.  
  283.     CLS
  284.     PRINT
  285.     PRINT
  286.     PRINT TAB(25);"Galilean Menu"
  287.     PRINT
  288.     PRINT
  289.     PRINT TAB(20);"< 1 > Display Data"
  290.     PRINT
  291.     PRINT TAB(20);"< 2 > Graphics"
  292.     PRINT
  293.     PRINT TAB(20);"< 3 > Continue"
  294.     PRINT
  295.     PRINT TAB(20);"< 4 > End"
  296.     PRINT
  297.     PRINT
  298.     PRINT "Selection"
  299.     INPUT SELECTION%
  300.  
  301. END SUB
  302.  
  303. '********************************************************************
  304.  
  305. SUB DISPLAY.DATA STATIC
  306.  
  307.     ' display data subroutine
  308.  
  309.     CLS
  310.     PRINT
  311.     PRINT TAB(5);"Calendar date";TAB(60-LEN(CDATE$));CDATE$
  312.     PRINT
  313.     PRINT TAB(5);"Local civil time";TAB(60-LEN(LCT$));LCT$
  314.     PRINT
  315.     PRINT TAB(5);"Julian Date";
  316.     PRINT TAB(48);
  317.     PRINT USING "########.###";JULIAN.DATE
  318.     PRINT
  319.     PRINT TAB(5);"Semidiameter ( arc seconds )";
  320.     PRINT TAB(48);
  321.     PRINT USING "########.###";SEMIDIAMETER
  322.     PRINT
  323.     PRINT
  324.     PRINT TAB(5);"Satellite       X-position       Y-position       Angle"
  325.     PRINT TAB(5);"---------       ----------       ----------       -----"
  326.     FOR I%=1 TO 4
  327.         A$=STR$(INT(U(I%)*RTD))
  328.         PRINT
  329.         PRINT TAB(5);SATELLITE$(I%);
  330.         PRINT TAB(22);
  331.         PRINT USING "###.###";X(I%);
  332.         PRINT TAB(39);
  333.         PRINT USING "###.###";Y(I%);
  334.         PRINT TAB(59-LEN(A$));A$
  335.     NEXT I%
  336.  
  337.     TDELAY=20
  338.     CALL KEYCHECK
  339.  
  340. END SUB
  341.  
  342. '********************************************************************
  343.  
  344. SUB GRAPHICS STATIC
  345.  
  346.     ' graphics subroutine
  347.  
  348.     SCREEN 2
  349.  
  350.     PRINT
  351.     PRINT TAB(5);CDATE$;
  352.     PRINT TAB(75-LEN(LCT$));LCT$
  353.     PRINT TAB(38);"North"
  354.     LOCATE 9,1
  355.     PRINT TAB(70);"West"
  356.     A$="JUPITER"
  357.     LOCATE 5,1
  358.     FOR J%=1 TO 7
  359.         PRINT TAB(40);MID$(A$,J%,1)
  360.     NEXT J%
  361.     CIRCLE (315,110),10
  362.     PAINT (315,110)
  363.     LOCATE 16,1
  364.     FOR I%=1 TO 4
  365.         X=315+10*X(I%)
  366.         Y=110-4.4444*Y(I%)
  367.         S$="^ "+SATELLITE$(I%)
  368.         CIRCLE (X,Y),5
  369.         PAINT (X,Y)
  370.         IF (X+LEN(S$))>550 THEN
  371.            S$=SATELLITE$(I%)+" ^"
  372.            X=X-7*LEN(S$)
  373.         END IF
  374.         PRINT TAB(X/8);S$
  375.     NEXT I%
  376.  
  377.     A=TIMER
  378.     B=TIMER+TDELAY
  379.     A$=""
  380.  
  381.     WHILE A$="" AND A<B
  382.       A=TIMER
  383.       A$=INKEY$
  384.     WEND
  385.  
  386.     SCREEN 0
  387.  
  388. END SUB
  389.  
  390. '********************************************************************
  391.  
  392. SUB INTRODUCTION STATIC
  393.  
  394.     ' program introduction subroutine
  395.  
  396.     CLS
  397.     TDELAY=30
  398.  
  399.     PRINT
  400.     PRINT
  401.     PRINT TAB(4);"GALILEAN is an interactive QuickBASIC program which can be"
  402.     PRINT TAB(4);"used to determine the position of the Galilean satellites"
  403.     PRINT TAB(4);"relative to Jupiter. This information is useful for such"
  404.     PRINT TAB(4);"activities as astronomical observations, astrophotography"
  405.     PRINT TAB(4);"and the study of occultations between the moons."
  406.     PRINT
  407.     PRINT TAB(4);"This program provides the position of each of the four"
  408.     PRINT TAB(4);"Galilean moons in the units of the radius of Jupiter. The"
  409.     PRINT TAB(4);"x-position of each satellite is measured positive west of"
  410.     PRINT TAB(4);"Jupiter and the y-position is measured positive north."
  411.     PRINT TAB(4);"It also calculates the 'position angle' of each satellite."
  412.     PRINT TAB(4);"This angle helps determine if any of the satellites are"
  413.     PRINT TAB(4);"in front of or behind Jupiter. A position angle near 0"
  414.     PRINT TAB(4);"or 360 degrees is called 'inferior conjunction' and an"
  415.     PRINT TAB(4);"angle near 180 degrees is called 'superior conjunction'."
  416.     PRINT TAB(4);"A satellite is in front of Jupiter at inferior conjunction"
  417.     PRINT TAB(4);"and behind Jupiter at superior conjunction."
  418.     CALL KEYCHECK
  419.  
  420.     CLS
  421.     PRINT
  422.     PRINT
  423.     PRINT TAB(4);"Inputs required by program 'GALILEAN' include the user's"
  424.     PRINT TAB(4);"observation date, the local time and time zone. The user"
  425.     PRINT TAB(4);"must also specify if Daylight Savings Time is in effect."
  426.     PRINT TAB(4);"The date is input in numerical format and the local time"
  427.     PRINT TAB(4);"in 24 hour format. The time zone will be an integer number"
  428.     PRINT TAB(4);"between 0 and 23."
  429.     PRINT
  430.     PRINT TAB(4);"The 'Galilean Menu' will allow the user to display the"
  431.     PRINT TAB(4);"data and/or graphics for the selected date. The 'Continue'"
  432.     PRINT TAB(4);"selection of this menu will calculate the information for"
  433.     PRINT TAB(4);"the next day. The user can then choose to display data or"
  434.     PRINT TAB(4);"and/or graphics for the new date. Please note that you can"
  435.     PRINT TAB(4);"print the data or graphics screen by pressing the <Shift>"
  436.     PRINT TAB(4);"<PrtSc> keys. The 'End' selection of the 'Galilean Menu'"
  437.     PRINT TAB(4);"will allow you to end the current session and select a new"
  438.     PRINT TAB(4);"date and/or time."
  439.     CALL KEYCHECK
  440. END SUB
  441.  
  442. '********************************************************************
  443.  
  444. SUB KEYCHECK STATIC
  445.  
  446.     ' check user response subroutine
  447.  
  448.     PRINT
  449.     PRINT
  450.     PRINT TAB(20);"< press any key to continue >"
  451.  
  452.     A=TIMER
  453.     B=TIMER+TDELAY
  454.     A$=""
  455.  
  456.     WHILE A$="" AND A<B
  457.       A=TIMER
  458.       A$=INKEY$
  459.     WEND
  460.  
  461. END SUB
  462.  
  463.